home *** CD-ROM | disk | FTP | other *** search
Text File | 1995-03-27 | 41.9 KB | 979 lines | [TEXT/ROSA] |
- Common Lisp the Language, 2nd Edition
- -------------------------------------------------------------------------------
-
- 4. Type Specifiers
-
- In Common Lisp, types are named by Lisp objects, specifically symbols and
- lists, called type specifiers. Symbols name predefined classes of objects,
- whereas lists usually indicate combinations or specializations of simpler
- types. Symbols or lists may also be abbreviations for types that could be
- specified in other ways.
-
- -------------------------------------------------------------------------------
-
- * Type Specifier Symbols
- * Type Specifier Lists
- * Predicating Type Specifiers
- * Type Specifiers That Combine
- * Type Specifiers That Specialize
- * Type Specifiers That Abbreviate
- * Defining New Type Specifiers
- * Type Conversion Function
- * Determining the Type of an Object
- * Type Upgrading
-
- -------------------------------------------------------------------------------
-
-
- 4.1 Type Specifier Symbols
-
- The type symbols defined by the system include those shown in table 4-1. In
- addition, when a structure type is defined using defstruct, the name of the
- structure type becomes a valid type symbol.
-
- [change_begin]
- Notice of correction. In the first edition, the type specifiers signed-byte and
- unsigned-byte were inadvertently omitted from table 4-1.
- [change_end]
-
- [change_begin]
- X3J13 voted in March 1989 (COMMON-TYPE) to eliminate the type common; this
- fact is indicated by the brackets around the common type specifier in the
- table.
-
- X3J13 voted in March 1989 (CHARACTER-PROPOSAL) to eliminate the type
- string-char; this fact is indicated by the brackets around the string-char type
- specifier in the table.
-
- X3J13 voted in March 1989 (CHARACTER-PROPOSAL) to add the type
- extended-character and the type base-character.
-
- X3J13 voted in March 1989 (REAL-NUMBER-TYPE) to add the type specifier real.
-
- X3J13 votes have also implicitly added many other type specifiers as names of
- classes (see chapter 28) or of conditions (see chapter 29).
- [change_end]
-
-
- 4.2. Type Specifier Lists
-
- If a type specifier is a list, the car of the list is a symbol, and the rest of
- the list is subsidiary type information. In many cases a subsidiary item may be
- unspecified. The unspecified subsidiary item is indicated by writing *. For
- example, to completely specify a vector type, one must mention the type of the
- elements and the length of the vector, as for example
-
- (vector double-float 100)
-
- To leave the length unspecified, one would write
-
- (vector double-float *)
-
- To leave the element type unspecified, one would write
-
- (vector * 100)
-
- [change_begin]
- One may also leave both length and element type unspecified:
-
- (vector * *)
-
- [change_end]
-
- Suppose that two type specifiers are the same except that the first has a *
- where the second has a more explicit specification. Then the second denotes a
- subtype of the type denoted by the first.
-
- As a convenience, if a list has one or more unspecified items at the end, such
- items may simply be dropped rather than writing an explicit * for each one. If
- dropping all occurrences of * results in a singleton list, then the parentheses
- may be dropped as well (the list may be replaced by the symbol in its car). For
- example, (vector double-float *) may be abbreviated to (vector double-float),
- and (vector * *) may be abbreviated to (vector) and then to simply vector.
-
-
- 4.3. Predicating Type Specifiers
-
- A type specifier list (satisfies predicate-name) denotes the set of all objects
- that satisfy the predicate named by predicate-name, which must be a symbol
- whose global function definition is a one-argument predicate. (A name is
- required; lambda-expressions are disallowed in order to avoid scoping
- problems.) For example, the type (satisfies numberp) is the same as the type
- number. The call (typep x '(satisfies p)) results in applying p to x and
- returning t if the result is true and nil if the result is false.
-
- [old_change_begin]
- As an example, the type string-char could be defined as
-
- (deftype string-char ()
- '(and character (satisfies string-char-p)))
-
- See deftype.
- [old_change_end]
-
- [change_begin]
- X3J13 voted in March 1989 (COMMON-TYPE) to remove the type string-char and
- the function string-char-p from the language.
- [change_end]
-
- It is not a good idea for a predicate appearing in a satisfies type specifier
- to cause any side effects when invoked.
-
-
- 4.4. Type Specifiers That Combine
-
- The following type specifier lists define a type in terms of other types or
- objects.
-
- (member object1 object2 ...)
- This denotes the set containing precisely those objects named. An object
- is of this type if and only if it is eql to one of the specified objects.
-
- -------------------------------------------------------------------------------
- Compatibility note: This is roughly equivalent to the Interlisp DECL package's
- memq.
- -------------------------------------------------------------------------------
-
- [change_begin]
-
- (eql object)
- X3J13 voted in June 1988 (CLOS) to add the eql type specifier. It may be
- used as a parameter specializer for CLOS methods (see section 28.1.6.2 and
- find-method). It denotes the set of the one object named; an object is of
- this type if and only if it is eql to object. While (eql object) denotes
- the same type as (member object), only (eql object) may be used as a CLOS
- parameter specializer.
-
- [change_end]
-
- (not type)
- This denotes the set of all those objects that are not of the specified
- type.
-
- (and type1 type2 ...)
- This denotes the intersection of the specified types.
-
- -------------------------------------------------------------------------------
- Compatibility note: This is roughly equivalent to the Interlisp DECL package's
- allof.
- -------------------------------------------------------------------------------
-
- When typep processes an and type specifier, it always tests each of the
- component types in order from left to right and stops processing as soon
- as one component of the intersection has been found to which the object in
- question does not belong. In this respect an and type specifier is similar
- to an executable and form. The purpose of this similarity is to allow a
- satisfies type specifier to depend on filtering by previous type
- specifiers. For example, suppose there were a function primep that takes
- an integer and says whether it is prime. Suppose also that it is an error
- to give any object other than an integer to primep. Then the type
- specifier
-
- (and integer (satisfies primep))
-
- is guaranteed never to result in an error because the function primep will
- not be invoked unless the object in question has already been determined
- to be an integer.
-
- (or type1 type2 ...)
- This denotes the union of the specified types. For example, the type list
- by definition is the same as (or null cons). Also, the value returned by
- the function position is always of type (or null (integer 0 *)) (either
- nil or a non-negative integer).
-
- -------------------------------------------------------------------------------
- Compatibility note: This is roughly equivalent to the Interlisp DECL package's
- oneof.
- -------------------------------------------------------------------------------
-
- As for and, when typep processes an or type specifier, it always tests
- each of the component types in order from left to right and stops
- processing as soon as one component of the union has been found to which
- the object in question belongs.
-
-
- 4.5. Type Specifiers That Specialize
-
- Some type specifier lists denote specializations of data types named by
- symbols. These specializations may be reflected by more efficient
- representations in the underlying implementation. As an example, consider the
- type (array short-float). Implementation A may choose to provide a specialized
- representation for arrays of short floating-point numbers, and implementation B
- may choose not to.
-
- If you should want to create an array for the express purpose of holding only
- short-float objects, you may optionally specify to make-array the element type
- short-float. This does not require make-array to create an object of type
- (array short-float); it merely permits it. The request is construed to mean
- ``Produce the most specialized array representation capable of holding
- short-floats that the implementation can provide.'' Implementation A will then
- produce a specialized array of type (array short-float), and implementation B
- will produce an ordinary array of type (array t).
-
- If one were then to ask whether the array were actually of type (array
- short-float), implementation A would say ``yes,'' but implementation B would
- say ``no.'' This is a property of make-array and similar functions: what you
- ask for is not necessarily what you get.
-
- [old_change_begin]
- Types can therefore be used for two different purposes: declaration and
- discrimination. Declaring to make-array that elements will always be of type
- short-float permits optimization. Similarly, declaring that a variable takes on
- values of type (array short-float) amounts to saying that the variable will
- take on values that might be produced by specifying element type short-float to
- make-array. On the other hand, if the predicate typep is used to test whether
- an object is of type (array short-float), only objects actually of that
- specialized type can satisfy the test; in implementation B no object can pass
- that test.
- [old_change_end]
-
- [change_begin]
- X3J13 voted in January 1989 (ARRAY-TYPE-ELEMENT-TYPE-SEMANTICS) to eliminate
- the differing treatment of types when used ``for discrimination'' rather than
- ``for declaration'' on the grounds that implementors have not treated the
- distinction consistently and (which is more important) users have found the
- distinction confusing.
-
- As a consequence of this change, the behavior of typep and subtypep on array
- and complex type specifiers must be modified. See the descriptions of those
- functions. In particular, under their new behavior, implementation B would say
- ``yes,'' agreeing with implementation A, in the discussion above.
-
- Note that the distinction between declaration and discrimination remains
- useful, if only so that we may remark that the specialized (list) form of the
- function type specifier may still be used only for declaration and not for
- discrimination.
-
- X3J13 voted in June 1988 (FUNCTION-TYPE) to clarify that while the
- specialized form of the function type specifier (a list of the symbol function
- possibly followed by argument and value type specifiers) may be used only for
- declaration, the symbol form (simply the name function) may be used for
- discrimination.
- [change_end]
-
- The valid list-format names for data types are as follows:
-
- (array element-type dimensions)
- This denotes the set of specialized arrays whose elements are all members
- of the type element-type and whose dimensions match dimensions. For
- declaration purposes, this type encompasses those arrays that can result
- by specifying element-type as the element type to the function make-array;
- this may be different from what the type means for discrimination
- purposes. element-type must be a valid type specifier or unspecified.
- dimensions may be a non-negative integer, which is the number of
- dimensions, or it may be a list of non-negative integers representing the
- length of each dimension (any dimension may be unspecified instead), or it
- may be unspecified. For example:
-
- (array integer 3) ;Three-dimensional arrays of integers
- (array integer (* * *)) ;Three-dimensional arrays of integers
- (array * (4 5 6)) ;4-by-5-by-6 arrays
- (array character (3 *)) ;Two-dimensional arrays of characters
- ; that have exactly three rows
- (array short-float ()) ;Zero-rank arrays of short-format
- ; floating-point numbers
-
- Note that (array t) is a proper subset of (array *). The reason is that
- (array t) is the set of arrays that can hold any Common Lisp object (the
- elements are of type t, which includes all objects). On the other hand,
- (array *) is the set of all arrays whatsoever, including, for example,
- arrays that can hold only characters. Now (array character) is not a
- subset of (array t); the two sets are in fact disjoint because (array
- character) is not the set of all arrays that can hold characters but
- rather the set of arrays that are specialized to hold precisely characters
- and no other objects. To test whether an array foo can hold a character,
- one should not use
-
- (typep foo '(array character))
-
- but rather
-
- (subtypep 'character (array-element-type foo))
-
- See array-element-type.
-
- [change_begin]
- X3J13 voted in January 1989 (ARRAY-TYPE-ELEMENT-TYPE-SEMANTICS) to
- change typep and subtypep so that the specialized array type specifier
- means the same thing for discrimination as for declaration: it encompasses
- those arrays that can result by specifying element-type as the element
- type to the function make-array. Under this interpretation (array
- character) might be the same type as (array t) (although it also might not
- be the same). See upgraded-array-element-type. However,
-
- (typep foo '(array character))
-
- is still not a legitimate test of whether the array foo can hold a
- character; one must still say
-
- (subtypep 'character (array-element-type foo))
-
- to determine that question.
-
- X3J13 also voted in January 1989 (DECLARE-ARRAY-TYPE-ELEMENT-REFERENCES)
- to specify that within the lexical scope of an array type declaration, it
- is an error for an array element, when referenced, not to be of the exact
- declared element type. A compiler may, for example, treat every reference
- to an element of a declared array as if the reference were surrounded by a
- the form mentioning the declared array element type (not the upgraded
- array element type). Thus
-
- (defun snarf-hex-digits (the-array)
- (declare (type (array (unsigned-byte 4) 1) the-array))
- (do ((j (- (length array) 1) (- j 1))
- (val 0 (logior (ash val 4)
- (aref the-array j))))
- ((< j 0) val)))
-
- may be treated as
-
- (defun snarf-hex-digits (the-array)
- (declare (type (array (unsigned-byte 4) 1) the-array))
- (do ((j (- (length array) 1) (- j 1))
- (val 0 (logior (ash val 4)
- (the (unsigned-byte 4)
- (aref the-array j)))))
- ((< j 0) val)))
-
- The declaration amounts to a promise by the user that the aref will never
- produce a value outside the interval 0 to 15, even if in that particular
- implementation the array element type (unsigned-byte 4) is upgraded to,
- say, (unsigned-byte 8). If such upgrading does occur, then values outside
- that range may in fact be stored in the-array, as long as the code in
- snarf-hex-digits never sees them.
-
- As a general rule, a compiler would be justified in transforming
-
- (aref (the (array elt-type ...) a) ...)
-
- into
-
- (the elt-type (aref (the (array elt-type ...) a) ...)
-
- It may also make inferences involving more complex functions, such as
- position or find. For example, find applied to an array always returns
- either nil or an object whose type is the element type of the array.
-
- [change_end]
-
- (simple-array element-type dimensions)
- This is equivalent to (array element-type dimensions) except that it
- additionally specifies that objects of the type are simple arrays (see
- section 2.5).
-
- (vector element-type size)
- This denotes the set of specialized one-dimensional arrays whose elements
- are all of type element-type and whose lengths match size. This is
- entirely equivalent to (array element-type (size)). For example:
-
- (vector double-float) ;Vectors of double-format
- ; floating-point numbers
- (vector * 5) ;Vectors of length 5
- (vector t 5) ;General vectors of length 5
- (vector (mod 32) *) ;Vectors of integers between 0 and 31
-
- [old_change_begin]
-
- The specialized types (vector string-char) and (vector bit) are so useful
- that they have the special names string and bit-vector. Every
- implementation of Common Lisp must provide distinct representations for
- these as distinct specialized data types.
-
- [old_change_end]
-
- [change_begin]
-
- X3J13 voted in March 1989 (CHARACTER-PROPOSAL) to eliminate the type
- string-char and to redefine the type string to be the union of one or more
- specialized vector types, the types of whose elements are subtypes of the
- type character.
-
- [change_end]
-
- (simple-vector size)
- This is the same as (vector t size) except that it additionally specifies
- that its elements are simple general vectors.
-
- (complex type)
- Every element of this type is a complex number whose real part and
- imaginary part are each of type type. For declaration purposes, this type
- encompasses those complex numbers that can result by giving numbers of the
- specified type to the function complex; this may be different from what
- the type means for discrimination purposes. As an example, Gaussian
- integers might be described as (complex integer), even in implementations
- where giving two integers to the function complex results in an object of
- type (complex rational).
-
- [change_begin]
-
- X3J13 voted in January 1989 (ARRAY-TYPE-ELEMENT-TYPE-SEMANTICS) to
- change typep and subtypep so that the specialized complex type specifier
- means the same thing for discrimination purposes as for declaration
- purposes. See upgraded-complex-part-type.
-
- [change_end]
-
- (function (arg1-type arg2-type ...) value-type)
- This type may be used only for declaration and not for discrimination;
- typep will signal an error if it encounters a specifier of this form.
- Every element of this type is a function that accepts arguments at least
- of the types specified by the argj-type forms and returns a value that is
- a member of the types specified by the value-type form. The &optional,
- &rest, and &key markers may appear in the list of argument types. The
- value-type may be a values type specifier in order to indicate the types
- of multiple values.
-
- [change_begin]
-
- X3J13 voted in January 1989 (FUNCTION-TYPE-REST-LIST-ELEMENT) to specify
- that the arg-type that follows a &rest marker indicates the type of each
- actual argument that would be gathered into the list for a &rest
- parameter, and not the type of the &rest parameter itself (which is always
- list). Thus one might declare the function gcd to be of type (function
- (&rest integer) integer), or the function aref to be of type (function
- (array &rest fixnum) t).
-
- X3J13 voted in March 1988 (FUNCTION-TYPE-KEY-NAME) to specify that, in a
- function type specifier, an argument type specifier following &key must be
- a list of two items, a keyword and a type specifier. The keyword must be a
- valid keyword-name symbol that may be supplied in the actual arguments of
- a call to the function, and the type specifier indicates the permitted
- type of the corresponding argument value. (The keyword-name symbol is
- typically a keyword, but another X3J13 vote
- (KEYWORD-ARGUMENT-NAME-PACKAGE) allows it to be any symbol.)
- Furthermore, if &allow-other-keys is not present, the set of keyword-names
- mentioned in the function type specifier may be assumed to be exhaustive;
- for example, a compiler would be justified in issuing a warning for a
- function call using a keyword argument name not mentioned in the type
- declaration for the function being called. If &allow-other-keys is present
- in the function type specifier, other keyword arguments may be supplied
- when calling a function of the indicated type, and if supplied such
- arguments may possibly be used.
-
- [change_end]
-
- [old_change_begin]
-
- As an example, the function cons is of type (function (t t) cons), because
- it can accept any two arguments and always returns a cons. The function
- cons is also of type (function (float string) list), because it can
- certainly accept a floating-point number and a string (among other
- things), and its result is always of type list (in fact a cons is never
- null, but that does not matter for this type declaration). The function
- truncate is of type (function (number number) (values number number)), as
- well as of type (function (integer (mod 8)) integer).
-
- [old_change_end]
-
- [change_begin]
-
- X3J13 voted in January 1989 (FUNCTION-TYPE-ARGUMENT-TYPE-SEMANTICS) to
- alter the meaning of the function type specifier when used in type and
- ftype declarations. While the preceding formulation may be theoretically
- elegant, they have found that it is not useful to compiler implementors
- and that it is not the interpretation that users expect. X3J13 prescribed
- instead the following interpretation of declarations.
-
- A declaration specifier of the form
-
- (ftype (function (arg1-type arg2-type ... argn-type) value-type) fname)
-
- implies that any function call of the form
-
- (fname arg1 arg2 ...)
-
- within the scope of the declaration can be treated as if it were rewritten
- to use the-forms in the following manner:
-
- (the value-type
- (fname (the arg1-type arg1)
- (the arg2-type arg2)
- ...
- (the argn-type argn)))
-
- That is, it is an error for any of the actual arguments not to be of its
- specified type arg-type or for the result not to be of the specified type
- value-type. (In particular, if any argument is not of its specified type,
- then the result is not guaranteed to be of the specified type-if indeed a
- result is returned at all.)
-
- Similarly, a declaration specifier of the form
-
- (type (function (arg1-type arg2-type ... argn-type) value-type) var)
-
- is interpreted to mean that any reference to the variable var will find
- that its value is a function, and that it is an error to call this
- function with any actual argument not of its specified type arg-type.
- Also, it is an error for the result not to be of the specified type
- value-type. For example, a function call of the form
-
- (funcall var arg1 arg2 ...)
-
- could be rewritten to use the-forms as well. If any argument is not of its
- specified type, then the result is not guaranteed to be of the specified
- type-if indeed a result is returned at all.
-
- Thus, a type or ftype declaration specifier describes type requirements
- imposed on calls to a function as opposed to requirements imposed on the
- definition of the function. This is analogous to the treatment of type
- declarations of variables as imposing type requirements on references to
- variables, rather than on the contents of variables. See the vote of X3J13
- on type declaration specifiers in general, discussed in section 9.2.
-
- In the same manner as for variable type declarations in general, if two or
- more of these declarations apply to the same function call (which can
- occur if declaration scopes are suitably nested), then they all apply; in
- effect, the types for each argument or result are intersected. For
- example, the code fragment
-
- (locally (declare (ftype (function (biped) digit)
- butcher-fudge))
- (locally (declare (ftype (function (featherless) opposable)
- butcher-fudge))
- (butcher-fudge sam)))
-
- may be regarded as equivalent to
-
- (the opposable
- (the digit (butcher-fudge (the featherless
- (the biped sam)))))
-
- or to
-
- (the (and opposable digit)
- (butcher-fudge (the (and featherless biped) sam)))
-
- That is, sam had better be both featherless and a biped, and the result of
- butcher-fudge had better be both opposable and a digit; otherwise the code
- is in error. Therefore a compiler may generate code that relies on these
- type assumptions, for example.
-
- [change_end]
-
- (values value1-type value2-type ...)
- This type specifier is extremely restricted: it may be used only as the
- value-type in a function type specifier or in a the special form. It is
- used to specify individual types when multiple values are involved. The
- &optional, &rest, and &key markers may appear in the value-type list; they
- thereby indicate the parameter list of a function that, when given to
- multiple-value-call along with the values, would be suitable for receiving
- those values.
-
-
- 4.6. Type Specifiers That Abbreviate
-
- The following type specifiers are, for the most part, abbreviations for other
- type specifiers that would be far too verbose to write out explicitly (using,
- for example, member).
-
- (integer low high)
- Denotes the integers between low and high. The limits low and high must
- each be an integer, a list of an integer, or unspecified. An integer is an
- inclusive limit, a list of an integer is an exclusive limit, and * means
- that a limit does not exist and so effectively denotes minus or plus
- infinity, respectively. The type fixnum is simply a name for (integer
- smallest largest) for implementation-dependent values of smallest and
- largest (see most-negative-fixnum and most-positive-fixnum). The type
- (integer 0 1) is so useful that it has the special name bit.
-
- (mod n)
- Denotes the set of non-negative integers less than n. This is equivalent
- to (integer 0 n-1) or to (integer 0 (n)).
-
- (signed-byte s)
- Denotes the set of integers that can be represented in two's-complement
- form in a byte of s bits. This is equivalent to (integer ). Simply
- signed-byte or (signed-byte *) is the same as integer.
-
- (unsigned-byte s)
- Denotes the set of non-negative integers that can be represented in a byte
- of s bits. This is equivalent to (mod ), that is, (integer 0 ). Simply
- unsigned-byte or (unsigned-byte *) is the same as (integer 0 *), the set
- of non-negative integers.
-
- (rational low high)
- Denotes the rationals between low and high. The limits low and high must
- each be a rational, a list of a rational, or unspecified. A rational is an
- inclusive limit, a list of a rational is an exclusive limit, and * means
- that a limit does not exist and so effectively denotes minus or plus
- infinity, respectively.
-
- (float low high)
- Denotes the set of floating-point numbers between low and high. The limits
- low and high must each be a floating-point number, a list of a
- floating-point number, or unspecified; a floating-point number is an
- inclusive limit, a list of a floating-point number is an exclusive limit,
- and * means that a limit does not exist and so effectively denotes minus
- or plus infinity, respectively.
-
- In a similar manner, one may use:
-
- (short-float low high)
- (single-float low high)
- (double-float low high)
- (long-float low high)
-
- In this case, if a limit is a floating-point number (or a list of one), it
- must be one of the appropriate format.
-
- [change_begin]
- X3J13 voted in March 1989 (REAL-NUMBER-TYPE) to add a list form of the real
- type specifier to denote an interval of real numbers.
-
- (real low high)
- Denotes the real numbers between low and high. The limits low and high
- must each be a real, a list of a real, or unspecified. A real is an
- inclusive limit, a list of a real is an exclusive limit, and * means that
- a limit does not exist and so effectively denotes minus or plus infinity,
- respectively.
-
- [change_end]
-
- [old_change_begin]
-
- (string size)
- Means the same as (array string-char (size)): the set of strings of the
- indicated size.
-
- (simple-string size)
- Means the same as (simple-array string-char (size)): the set of simple
- strings of the indicated size.
-
- [old_change_end]
-
- [change_begin]
- X3J13 voted in March 1989 (CHARACTER-PROPOSAL) to eliminate the type
- string-char and to redefine the type string to be the union of one or more
- specialized vector types, the types of whose elements are subtypes of the type
- character. Similarly, the type simple-string is redefined to be the union of
- one or more specialized simple vector types, the types of whose elements are
- subtypes of the type character.
-
- (base-string size)
- Means the same as (vector base-character size): the set of base strings of
- the indicated size.
-
- (simple-base-string size)
- Means the same as (simple-array base-character (size)): the set of simple
- base strings of the indicated size.
-
- [change_end]
-
- (bit-vector size)
- Means the same as (array bit (size)): the set of bit-vectors of the
- indicated size.
-
- (simple-bit-vector size)
- This means the same as (simple-array bit (size)): the set of bit-vectors
- of the indicated size.
-
-
- 4.7. Defining New Type Specifiers
-
- New type specifiers can come into existence in two ways. First, defining a new
- structure type with defstruct automatically causes the name of the structure to
- be a new type specifier symbol. Second, the deftype special form can be used to
- define new type-specifier abbreviations.
-
- [Macro]
- deftype name lambda-list [[{declaration}* | doc-string]] {form}*
-
- This is very similar to a defmacro form: name is the symbol that identifies the
- type specifier being defined, lambda-list is a lambda-list (and may contain
- &optional and &rest markers), and the forms constitute the body of the expander
- function. If we view a type specifier list as a list containing the type
- specifier name and some argument forms, the argument forms (unevaluated) are
- bound to the corresponding parameters in lambda-list. Then the body forms are
- evaluated as an implicit progn, and the value of the last form is interpreted
- as a new type specifier for which the original specifier was an abbreviation.
- The name is returned as the value of the deftype form.
-
- deftype differs from defmacro in that if no initform is specified for an
- &optional parameter, the default value is *, not nil.
-
- If the optional documentation string doc-string is present, then it is attached
- to the name as a documentation string of type type; see documentation.
-
- Here are some examples of the use of deftype:
-
- (deftype mod (n) `(integer 0 (,n)))
- (deftype list () '(or null cons))
-
- (deftype square-matrix (&optional type size)
- "SQUARE-MATRIX includes all square two-dimensional arrays."
- `(array ,type (,size ,size)))
-
- (square-matrix short-float 7) means (array short-float (7 7))
-
- (square-matrix bit) means (array bit (* *))
-
- If the type name defined by deftype is used simply as a type specifier symbol,
- it is interpreted as a type specifier list with no argument forms. Thus, in the
- example above, square-matrix would mean (array * (* *)), the set of
- two-dimensional arrays. This would unfortunately fail to convey the constraint
- that the two dimensions be the same; (square-matrix bit) has the same problem.
- A better definition is
-
- (defun equidimensional (a)
- (or (< (array-rank a) 2)
- (apply #'= (array-dimensions a))))
-
- (deftype square-matrix (&optional type size)
- `(and (array ,type (,size ,size))
- (satisfies equidimensional)))
-
- [change_begin]
- X3J13 voted in March 1988 (FLET-IMPLICIT-BLOCK) to specify that the body of
- the expander function defined by deftype is implicitly enclosed in a block
- construct whose name is the same as the name of the defined type. Therefore
- return-from may be used to exit from the function.
-
- X3J13 voted in March 1989 (DEFINING-MACROS-NON-TOP-LEVEL) to clarify that,
- while defining forms normally appear at top level, it is meaningful to place
- them in non-top-level contexts; deftype must define the expander function
- within the enclosing lexical environment, not within the global environment.
- [change_end]
-
-
- 4.8. Type Conversion Function
-
- The following function may be used to convert an object to an equivalent object
- of another type.
-
- [Function]
- coerce object result-type
-
- The result-type must be a type specifier; the object is converted to an
- ``equivalent'' object of the specified type. If the coercion cannot be
- performed, then an error is signaled. In particular, (coerce x 'nil) always
- signals an error. If object is already of the specified type, as determined by
- typep, then it is simply returned. It is not generally possible to convert any
- object to be of any type whatsoever; only certain conversions are permitted:
-
- * Any sequence type may be converted to any other sequence type, provided
- the new sequence can contain all actual elements of the old sequence (it
- is an error if it cannot). If the result-type is specified as simply
- array, for example, then (array t) is assumed. A specialized type such as
- string or (vector (complex short-float)) may be specified; of course, the
- result may be of either that type or some more general type, as determined
- by the implementation. Elements of the new sequence will be eql to
- corresponding elements of the old sequence. If the sequence is already of
- the specified type, it may be returned without copying it; in this,
- (coerce sequence type) differs from (concatenate type sequence), for the
- latter is required to copy the argument sequence. In particular, if one
- specifies sequence, then the argument may simply be returned if it already
- is a sequence.
-
- (coerce '(a b c) 'vector) => #(a b c)
-
- [change_begin]
- X3J13 voted in June 1989 (SEQUENCE-TYPE-LENGTH) to specify that coerce should
- signal an error if the new sequence type specifies the number of elements and
- the old sequence has a different length.
-
- X3J13 voted in March 1989 (CHARACTER-PROPOSAL) to specify that if the
- result-type is string then it is understood to mean (vector character), and
- simple-string is understood to mean (simple-array character (*)).
- [change_end]
-
- [old_change_begin]
-
- * Some strings, symbols, and integers may be converted to characters. If
- object is a string of length 1, then the sole element of the string is
- returned. If object is a symbol whose print name is of length 1, then the
- sole element of the print name is returned. If object is an integer n,
- then (int-char n) is returned. See character.
-
- (coerce "a" 'character) => #\a
-
- [old_change_end]
-
- [change_begin]
- X3J13 voted in March 1989 (CHARACTER-PROPOSAL) to eliminate int-char from
- Common Lisp. Presumably this eliminates the possibility of coercing an integer
- to a character, although the vote did not address this question directly.
- [change_end]
-
- * Any non-complex number can be converted to a short-float, single-float,
- double-float, or long-float. If simply float is specified, and object is
- not already a float of some kind, then the object is converted to a
- single-float.
-
- (coerce 0 'short-float) => 0.0S0
- (coerce 3.5L0 'float) => 3.5L0
- (coerce 7/2 'float) => 3.5
-
- * Any number can be converted to a complex number. If the number is not
- already complex, then a zero imaginary part is provided by coercing the
- integer zero to the type of the given real part. (If the given real part
- is rational, however, then the rule of canonical representation for
- complex rationals will result in the immediate re-conversion of the result
- from type complex back to type rational.)
-
- (coerce 4.5s0 'complex) => #C(4.5S0 0.0S0)
- (coerce 7/2 'complex) => 7/2
- (coerce #C(7/2 0) '(complex double-float))
- => #C(3.5D0 0.0D0)
-
- * Any object may be coerced to type t.
-
- (coerce x 't) == (identity x) == x
-
- [change_begin]
- X3J13 voted in June 1988 (FUNCTION-TYPE) to allow coercion of certain objects
- to the type function:
-
- * A symbol or lambda-expression can be converted to a function. A symbol is
- coerced to type function as if by applying symbol-function to the symbol;
- an error is signaled if the predicate fboundp is not true of the symbol or
- if the symbol names a macro or special form. A list x whose car is the
- symbol lambda is coerced to a function as if by execution of (eval `#',x),
- that is, of (eval (list 'function x)).
-
- [change_end]
-
- Coercions from floating-point numbers to rationals and from ratios to integers
- are purposely not provided because of rounding problems. The functions
- rational, rationalize, floor, ceiling, truncate, and round may be used for such
- purposes. Similarly, coercions from characters to integers are purposely not
- provided; char-code or char-int may be used explicitly to perform such
- conversions.
-
-
- 4.9. Determining the Type of an Object
-
- The following function may be used to obtain a type specifier describing the
- type of a given object.
-
- [Function]
- type-of object
-
- [old_change_begin]
- (type-of object) returns an implementation-dependent result: some type of which
- the object is a member. Implementors are encouraged to arrange for type-of to
- return the most specific type that can be conveniently computed and is likely
- to be useful to the user. If the argument is a user-defined named structure
- created by defstruct, then type-of will return the type name of that structure.
- Because the result is implementation-dependent, it is usually better to use
- type-of primarily for debugging purposes; however, in a few situations portable
- code requires the use of type-of, such as when the result is to be given to the
- coerce or map function. On the other hand, often the typep function or the
- typecase construct is more appropriate than type-of.
- [old_change_end]
-
- -------------------------------------------------------------------------------
- Compatibility note: In MacLisp the function type-of is called typep, and
- anomalously so, for it is not a predicate.
- -------------------------------------------------------------------------------
-
- [change_begin]
- Many have observed (and rightly so) that this specification is totally wimpy
- and therefore nearly useless. X3J13 voted in June 1989
- (TYPE-OF-UNDERCONSTRAINED) to place the following constraints on type-of:
-
- * Let x be an object such that (typep x type) is true and type is one of
- the following:
-
- array float package sequence
- bit-vector function pathname short-float
- character hash-table random-state single-float
- complex integer ratio stream
- condition long-float rational string
- cons null readtable symbol
- double-float number restart vector
-
- Then (subtypep (type-of x) type)) must return the values t and t; that is,
- type-of applied to x must return either type itself or a subtype of type
- that subtypep can recognize in that implementation.
-
- * For any object x, (subtypep (type-of x) (class-of x)) must produce the
- values t and t.
-
- * For every object x, (typep x (type-of x)) must be true. (This implies
- that type-of can never return nil, for no object is of type nil.)
-
- * type-of never returns t and never uses a satisfies, and, or, not, or
- values type specifier in its result.
-
- * For objects of CLOS metaclass structure-class or of standard-class,
- type-of returns the proper name of the class returned by class-of if it
- has a proper name, and otherwise returns the class itself. In particular,
- for any object created by a defstruct constructor function, where the
- defstruct had the name name and no :type option, type-of will return name.
-
- As an example, (type-of "acetylcholinesterase") may return string or
- simple-string or (simple-string 20), but not array or simple-vector. As another
- example, it is permitted for (type-of 1729) to return integer or fixnum (if it
- is indeed a fixnum) or (signed-byte 16) or (integer 1729 1729) or (integer 1685
- 1750) or even (mod 1730), but not rational or number, because
-
- (typep (+ (expt 9 3) (expt 10 3)) 'integer)
-
- is true, integer is in the list of types mentioned above, and
-
- (subtypep (type-of (+ (expt 1 3) (expt 12 3))) 'integer)
-
- would be false if type-of were to return rational or number.
- [change_end]
-
-
- [change_begin]
-
- 4.10. Type Upgrading
-
- X3J13 voted in January 1989 (ARRAY-TYPE-ELEMENT-TYPE-SEMANTICS) to add new
- functions by which a program can determine, in a given Common Lisp
- implementation, how that implementation will upgrade a type when constructing
- an array specialized to contain elements of that type, or a complex number
- specialized to contain parts of that type.
-
- [Function]
- upgraded-array-element-type type
-
- A type specifier is returned, indicating the element type of the most
- specialized array representation capable of holding items of the specified
- argument type. The result is necessarily a supertype of the given type.
- Furthermore, if a type A is a subtype of type B, then
- (upgraded-array-element-type A) is a subtype of (upgraded-array-element-type
- B).
-
- The manner in which an array element type is upgraded depends only on the
- element type as such and not on any other property of the array such as size,
- rank, adjustability, presence or absence of a fill pointer, or displacement.
-
- -------------------------------------------------------------------------------
- Rationale: If upgrading were allowed to depend on any of these properties, all
- of which can be referred to, directly or indirectly, in the language of type
- specifiers, then it would not be possible to displace an array in a consistent
- and dependable manner to another array created with the same :element-type
- argument but differing in one of these properties.
- -------------------------------------------------------------------------------
-
- Note that upgraded-array-element-type could be defined as
-
- (defun upgraded-array-element-type (type)
- (array-element-type (make-array 0 :element-type type)))
-
- but this definition has the disadvantage of allocating an array and then
- immediately discarding it. The clever implementor surely can conjure up a more
- practical approach.
-
- [Function]
- upgraded-complex-part-type type
-
- A type specifier is returned, indicating the element type of the most
- specialized complex number representation capable of having parts of the
- specified argument type. The result is necessarily a supertype of the given
- type. Furthermore, if a type A is a subtype of type B, then
- (upgraded-complex-part-type A) is a subtype of (upgraded-complex-part-type B).
- [change_end]
-
-
-
-
-
-
-
-
-
-